home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Shareware Grab Bag
/
Shareware Grab Bag.iso
/
001
/
pibt40s1.arc
/
EXECUTC1.MOD
< prev
next >
Wrap
Text File
|
1987-07-19
|
47KB
|
1,233 lines
(*----------------------------------------------------------------------*)
(* Execute_Command --- Execute PibTerm command *)
(*----------------------------------------------------------------------*)
PROCEDURE Execute_Command;
(*----------------------------------------------------------------------*)
(* *)
(* Procedure: Execute_Command *)
(* *)
(* Purpose: Execute PibTerm Commands *)
(* *)
(* Calling Sequence: *)
(* *)
(* Execute_Command( VAR Command : Pibterm_Command_Type; *)
(* VAR Done : BOOLEAN; *)
(* Use_Script : BOOLEAN ); *)
(* *)
(* Command --- Command to execute *)
(* Done --- set TRUE if termination command found *)
(* Use_Script --- TRUE if this is a script command execution *)
(* *)
(* Calls: Async_Send_String *)
(* PibDialer *)
(* Async_Send_Break *)
(* Async_Carrier_Detect *)
(* Display_Commands *)
(* Delay *)
(* GetAreaCode *)
(* PibUpLoad *)
(* PibDownLoad *)
(* Save_Screen *)
(* Restore_Screen *)
(* Draw_Menu_Frame *)
(* Fast_Change_Params *)
(* PibFileManipulation *)
(* Get_Capture_File *)
(* Toggle_Option *)
(* HangUpPhone *)
(* Send_Function_Key *)
(* Set_Input_Keys *)
(* Set_Translate_Table *)
(* Do_Screen_Dump *)
(* DosJump *)
(* Handle_Function_Key *)
(* *)
(*----------------------------------------------------------------------*)
VAR
Flag : BOOLEAN;
I : INTEGER;
J : INTEGER;
T_Type : Terminal_Type;
TimeW : STRING[8];
TimeN : STRING[8];
TimeO : STRING[8];
Local_Save : Saved_Screen_Ptr;
ESC_Found : BOOLEAN;
Trans_Type : Transfer_Type;
Ch : CHAR;
Rem_Ch : CHAR;
XPos : INTEGER;
GotChar : BOOLEAN;
S : AnyStr;
Echo : BOOLEAN;
Test_Cond : BOOLEAN;
File_Done : BOOLEAN;
Do_Editing : BOOLEAN;
Do_Viewing : BOOLEAN;
F : FILE;
Alter_Status : BOOLEAN;
VAR
Save_Do_Status_Line : BOOLEAN;
(* STRUCTURED *) CONST
Oper_Type_Vector : ARRAY[0..MaxOperandTypes] OF OperandType =
( Bad_Operand_Type, Operator_Type, Integer_Variable_Type,
Real_Variable_Type, String_Variable_Type,
Integer_Constant_Type, Real_Constant_Type,
String_Constant_Type,
StackEnd_Type, Left_Paren_Type, Right_Paren_Type );
LABEL
LAddLFSy, LAlarmSy, LAreaCodeSy, LBreakSy,
LCallSy, LCaptureSy, LChDirSy, LClearSy,
LCloseSy, LClrEolSy, LCommFlushSy, LDeclareSy,
LDelaySy, LDelLineSy, LDialSy, LDosSy,
LEchoSy, LEditSy, LExecuteSy, LExeNewSy,
LExitSy, LExitAllSy, LFastCSy, LFileSy,
LGetDirSy, LGetParamSy, LGetVarSy, LGossipSy,
LGoToSy, LGoToXYSy, LHangUpSy, LHostSy,
LIfConSy, LIfDialSy, LIfEofSy, LIfExistsSy,
LIfFoundSy, LIfLocStrSy, LIfOkSy, LIfOpSy,
LIfRemStrSy, LImportSy, LInfoSy, LInputSy,
LInsLineSy, LKeyDefSy, LKeyFlushSy, LKeySendSy,
LKeySy, LLogSy, LMenuSy, LMessageSy,
LMuteSy,
LOpenSy, LParamSy, LPImportSy, LQuitSy,
LReadSy, LReadLnSy, LReceiveSy, LReDialSy,
LResetSy, LReturnSy, LRInputSy, LScriptSy,
LSDumpSy, LSendSy, LSetSy, LSetVarSy,
LSTextSy,
LTextSy, LTimersSy, LTranslateSy, LViewSy,
LWaitSy, LWhereXYSy, LWriteSy, LWriteLnSy,
LWriteLogSy, LZapVarSy, LSetParamSy,
LEndCase;
{
PROCEDURE Debug_Write( S : AnyStr );
BEGIN (* Debug_Write *)
Write_Log( S , FALSE );
END (* Debug_Write *);
FUNCTION ITOS( I: INTEGER ) : AnyStr;
VAR
S: STRING[10];
BEGIN (* ITOS *)
STR( I , S );
ITOS := S;
END (* ITOS *);
}
(*----------------------------------------------------------------------*)
(* Remote_Input --- get remote input in response to prompt *)
(*----------------------------------------------------------------------*)
PROCEDURE Remote_Input;
(*----------------------------------------------------------------------*)
(* *)
(* Procedure: Remote_Input *)
(* *)
(* Purpose: Gets remote input (from host system) in response to *)
(* prompt. *)
(* *)
(* Calling Sequence: *)
(* *)
(* Remote_Input; *)
(* *)
(* Global string -Script_Remote_Reply- get the resultant *)
(* input. *)
(* *)
(* Calls: Async_Send *)
(* Send_Function_Key *)
(* Async_Receive *)
(* *)
(*----------------------------------------------------------------------*)
VAR
Rem_Ch : CHAR;
XPos : INTEGER;
GotChar : BOOLEAN;
S : AnyStr;
Echo : BOOLEAN;
Ch : CHAR;
BEGIN (* Remote_Input *)
(* Send prompt to remote system *)
IF LENGTH( Script_String ) > 0 THEN
Send_Function_Key( Read_Ctrls( Script_String ) );
Ch := CHR( 0 );
Script_Remote_Reply[0] := CHR( 0 );
XPos := WhereX;
Echo := ( Script_Integer_1 > 0 );
(* Get response string *)
REPEAT
GotChar := FALSE;
(* Check for keyboard input *)
IF KeyPressed THEN
BEGIN
READ( Kbd, Ch );
GotChar := TRUE;
END;
(* Check for remote input *)
IF Async_Receive( Rem_Ch ) THEN
BEGIN
Ch := Rem_Ch;
GotChar := TRUE;
END;
(* Process received character *)
IF GotChar THEN
IF Ch <> CHR( CR ) THEN
IF Ch = ^H THEN
BEGIN (* Backspace *)
IF WhereX > Xpos THEN
BEGIN
Async_Send( Ch );
WRITE( Ch );
Async_Send( ' ' );
WRITE( ' ' );
Async_Send( Ch );
WRITE( Ch );
IF ( LENGTH( Script_Remote_Reply ) > 1 ) THEN
Script_Remote_Reply := COPY( Script_Remote_Reply,
1,
LENGTH( Script_Remote_Reply ) - 1 )
ELSE
Script_Remote_Reply[0] := CHR( 0 );
END;
END (* Backspace *)
ELSE
BEGIN
Script_Remote_Reply := Script_Remote_Reply + Ch;
IF Echo THEN
BEGIN
Async_Send( Ch );
WRITE( Ch );
END
ELSE
BEGIN
Async_Send( '.' );
WRITE( '.' );
END
END;
UNTIL ( Ch = CHR( CR ) ) OR ( NOT Async_Carrier_Detect );
Script_Remote_Reply_Ok := FALSE;
(* Copy to variable if necessary *)
IF ( Script_Integer_2 > 2 ) THEN
Script_Variables^[Script_Integer_2].Var_Value^ :=
Script_Remote_Reply;
END (* Remote_Input *);
(*----------------------------------------------------------------------*)
(* Execute_Stack --- Execute postfix command stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Execute_Stack( Result_Index : INTEGER );
VAR
Stack : ARRAY[1..MaxExecStack] OF Stack_Entry_Ptr;
End_Of_Stack : BOOLEAN;
Stack_Index : INTEGER;
Operand_Type : INTEGER;
Index : INTEGER;
Var_Ptr : Stack_Entry_Ptr;
IVal : INTEGER;
Int1 : INTEGER;
Str1 : AnyStr;
Int1_Bytes : ARRAY[1..2] OF BYTE ABSOLUTE Int1;
(*----------------------------------------------------------------------*)
(* Move_Variable_To_Stack --- Place variable on evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Move_Variable_To_Stack( Index : INTEGER );
VAR
IType : OperandType;
BEGIN (* Move_Variable_To_Stack *)
Stack_Index := SUCC( Stack_Index );
NEW( Stack[Stack_Index] );
(* Defines a script record *)
IType := Script_Variables^[Index].Var_Type;
Stack[Stack_Index]^.TypVal := IType;
CASE IType OF
Integer_Variable_Type: MOVE( Script_Variables^[Index].Var_Value^[1],
Stack[Stack_Index]^.IntVal, 2 );
String_Variable_Type : Stack[Stack_Index]^.StrVal := Script_Variables^[Index].Var_Value^;
END (* CASE *);
END (* Move_Variable_To_Stack *);
(*----------------------------------------------------------------------*)
(* Move_Integer_Constant_To_Stack --- Place integer on evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Move_Integer_Constant_To_Stack( IntVal : INTEGER );
BEGIN (* Move_Integer_Constant_To_Stack *)
Stack_Index := SUCC( Stack_Index );
NEW( Stack[Stack_Index] );
Stack[Stack_Index]^.TypVal := Integer_Variable_Type;
Stack[Stack_Index]^.IntVal := IntVal;
END (* Move_Integer_Constant_To_Stack *);
(*----------------------------------------------------------------------*)
(* Move_String_Constant_To_Stack --- Place string on evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Move_String_Constant_To_Stack( VAR Index : INTEGER );
VAR
L : INTEGER;
BEGIN (* Move_String_Constant_To_Stack *)
Stack_Index := SUCC( Stack_Index );
NEW( Stack[Stack_Index] );
L := Script_Buffer^[Index];
MOVE( Script_Buffer^[Index+1], Stack[Stack_Index]^.StrVal[1], L );
Stack[Stack_Index]^.StrVal[0] := CHR( L );
Stack[Stack_Index]^.TypVal := String_Variable_Type;
Index := Index + L;
{
IF Debug_Mode THEN
Debug_Write('===> Moving <' + Stack[Stack_Index]^.StrVal + '> onto stack.');
}
END (* Move_String_Constant_To_Stack *);
(*----------------------------------------------------------------------*)
(* Pop_Stack_Integer --- Remove integer from evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Pop_Stack_Integer( VAR IntVal : INTEGER );
BEGIN (* Pop_Stack_Integer *)
IntVal := Stack[Stack_Index]^.IntVal;
DISPOSE( Stack[Stack_Index] );
Stack_Index := PRED( Stack_Index );
END (* Pop_Stack_Integer *);
(*----------------------------------------------------------------------*)
(* Pop_Stack_String --- Remove string from evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Pop_Stack_String( VAR StrVal : AnyStr );
BEGIN (* Pop_Stack_String *)
StrVal := Stack[Stack_Index]^.StrVal;
DISPOSE( Stack[Stack_Index] );
Stack_Index := PRED( Stack_Index );
END (* Pop_Stack_String *);
(*----------------------------------------------------------------------*)
(* Perform_Operator --- Execute operator using evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Perform_Operator( Operator : OperType );
VAR
Int1: INTEGER;
Int2: INTEGER;
Str1: AnyStr;
Str2: AnyStr;
Str3: AnyStr;
IRes: INTEGER;
SRes: AnyStr;
I : INTEGER;
Int1_Bytes : ARRAY[1..2] OF BYTE ABSOLUTE Int1;
TYPE
ArgType = ( One_String, One_Integer, Two_Integers, Two_Strings,
String_And_One_Integer, String_And_Two_Integers,
Special_Args, No_Args );
(* STRUCTURED *) CONST
ArgTypeVector : ARRAY[OperType] OF ArgType =
( Special_Args, Two_Integers, Two_Integers, Two_Integers,
Two_Integers, Two_Integers, Two_Integers, Two_Integers,
Two_Integers, Two_Integers, Two_Integers,
Two_Strings, Two_Strings, Two_Strings,
Two_Strings, Two_Strings, Two_Strings,
Two_Integers,
One_Integer, Two_Integers, Two_Integers,
String_And_Two_Integers, Two_Strings, One_String,
Two_Strings, No_Args, No_Args, One_Integer,
One_String, No_Args, One_String , One_Integer ,
No_Args, String_And_One_Integer, One_String, One_String,
No_Args, One_Integer, No_Args, No_Args, One_String,
No_Args, No_Args, One_Integer, String_And_One_Integer,
One_Integer, One_String, One_String );
ResTypeVector : ARRAY[OperType] OF OperandType =
( Bad_Operand_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
String_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, String_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
String_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
Integer_Variable_Type, Integer_Variable_Type,
String_Variable_Type, String_Variable_Type,
String_Variable_Type, Integer_Variable_Type,
String_Variable_Type, String_Variable_Type,
Integer_Variable_Type, String_Variable_Type,
String_Variable_Type, String_Variable_Type,
String_Variable_Type, Integer_Variable_Type,
String_Variable_Type, String_Variable_Type,
String_Variable_Type );
LABEL
LNoOpSy, LAddSy, LSubtractSy, LMultSy, LDivideSy,
LEqualISy, LLessISy, LLessEqualISy, LGreaterISy, LGreaterEqualISy,
LNotEqualISy, LEqualSSy, LLessSSy, LLessEqualSSy, LGreaterSSy,
LGreaterEqualSSy, LNotEqualSSy, LAndSy, LNotSy, LOrSy,
LXorSy, LSubStrSy, LIndexSy, LLengthSy, LConcatSy,
LConnectedSy, LWaitFoundSy, LStringSy, LNumberSy, LAttendedSy,
LFileExistsSy, LEofSy, LIOResultSy, LDuplSy, LUpperCaseSy,
LTrimSy, LParamCountSy, LParamStrSy, LParamLineSy, LDialedSy,
LLTrimSy, LDateSy, LTimeSy, LDialEntrySy, LOrdSy,
LChrSy, LReadCtrlSy, LWriteCtrlSy, LEndCase;
(*----------------------------------------------------------------------*)
(* Push_Stack_Integer --- Push integer value onto evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Push_Stack_Integer( IntVal : INTEGER );
BEGIN (* Push_Stack_Integer *)
Stack_Index := SUCC( Stack_Index );
NEW( Stack[Stack_Index] );
Stack[Stack_Index]^.TypVal := Integer_Variable_Type;
Stack[Stack_Index]^.IntVal := IntVal;
END (* Push_Stack_Integer *);
(*----------------------------------------------------------------------*)
(* Push_Stack_String --- Push string value onto evaluation stack *)
(*----------------------------------------------------------------------*)
PROCEDURE Push_Stack_String( StrVal : AnyStr );
BEGIN (* Push_Stack_String *)
Stack_Index := SUCC( Stack_Index );
NEW( Stack[Stack_Index] );
Stack[Stack_Index]^.TypVal := String_Variable_Type;
Stack[Stack_Index]^.StrVal := StrVal;
{
IF Debug_Mode THEN
Debug_Write('===> Pushing <' + StrVal + '> onto stack.');
}
END (* Push_Stack_String *);
(*----------------------------------------------------------------------*)
BEGIN (* Perform_Operator *)
CASE ArgTypeVector[Operator] OF
One_String : Pop_Stack_String ( Str1 );
One_Integer : Pop_Stack_Integer( Int1 );
Two_Integers : BEGIN
Pop_Stack_Integer( Int2 );
Pop_Stack_Integer( Int1 );
END;
Two_Strings : BEGIN
Pop_Stack_String ( Str2 );
Pop_Stack_String ( Str1 );
END;
String_And_One_Integer : BEGIN
Pop_Stack_Integer( Int1 );
Pop_Stack_String ( Str1 );
END;
String_And_Two_Integers : BEGIN
Pop_Stack_Integer( Int2 );
Pop_Stack_Integer( Int1 );
Pop_Stack_String ( Str1 );
END;
ELSE;
END;
{ CASE Operator OF }
(* Use jump table to avoid time-consuming *)
(* CASE statement. *)
I := ORD( Operator );
INLINE(
$8B/$9E/>I { MOV BX,[BP+>I] ;Pick up ORD(Operator)}
/$89/$D8 { MOV AX,BX ;Command}
/$D1/$E3 { SHL BX,1 ;Command * 2}
/$01/$C3 { ADD BX,AX ;Command * 3}
/$B8/>*+6 { MOV AX,>*+6 ;Address of first GOTO}
/$01/$C3 { ADD BX,AX ;Add offset of command}
/$FF/$E3 { JMP BX ;Branch to proper GOTO}
);
GOTO LNoOpSy;
GOTO LAddSy;
GOTO LSubtractSy;
GOTO LMultSy;
GOTO LDivideSy;
GOTO LEqualISy;
GOTO LLessISy;
GOTO LLessEqualISy;
GOTO LGreaterISy;
GOTO LGreaterEqualISy;
GOTO LNotEqualISy;
GOTO LEqualSSy;
GOTO LLessSSy;
GOTO LLessEqualSSy;
GOTO LGreaterSSy;
GOTO LGreaterEqualSSy;
GOTO LNotEqualSSy;
GOTO LAndSy;
GOTO LNotSy;
GOTO LOrSy;
GOTO LXorSy;
GOTO LSubStrSy;
GOTO LIndexSy;
GOTO LLengthSy;
GOTO LConcatSy;
GOTO LConnectedSy;
GOTO LWaitFoundSy;
GOTO LStringSy;
GOTO LNumberSy;
GOTO LAttendedSy;
GOTO LFileExistsSy;
GOTO LEofSy;
GOTO LIOResultSy;
GOTO LDuplSy;
GOTO LUpperCaseSy;
GOTO LTrimSy;
GOTO LParamCountSy;
GOTO LParamStrSy;
GOTO LParamLineSy;
GOTO LDialedSy;
GOTO LLTrimSy;
GOTO LDateSy;
GOTO LTimeSy;
GOTO LDialEntrySy;
GOTO LOrdSy;
GOTO LChrSy;
GOTO LReadCtrlSy;
GOTO LWriteCtrlSy;
LNoOpSy : ;
GOTO LEndCase;
LAddSy: IRes := Int1 + Int2;
GOTO LEndCase;
LSubtractSy: IRes := Int1 - Int2;
GOTO LEndCase;
LMultSy: IRes := Int1 * Int2;
GOTO LEndCase;
LDivideSy: IF ( Int2 <> 0 ) THEN
IRes := Int1 DIV Int2
ELSE
IRes := 0;
GOTO LEndCase;
LConcatSy: BEGIN
IRes := ORD( Str1[0] ) + ORD( Str2[0] );
IF ( IRes <= 255 ) THEN
SRes := Str1 + Str2
ELSE
SRes := Str1 + Substr( Str2, 1, 255 - ORD( Str1[0] ) );
END;
GOTO LEndCase;
LSubStrSy: SRes := Substr( Str1, Int1, Int2 );
GOTO LEndCase;
LIndexSy: IRes := POS( Str1, Str2 );
GOTO LEndCase;
LLengthSy: IRes := ( ORD( Str1[0] ) );
GOTO LEndCase;
LEqualISy: IRes := ORD( Int1 = Int2 );
GOTO LEndCase;
LLessEqualISy: IRes := ORD( Int1 <= Int2 );
GOTO LEndCase;
LLessISy: IRes := ORD( Int1 < Int2 );
GOTO LEndCase;
LGreaterISy: IRes := ORD( Int1 > Int2 );
GOTO LEndCase;
LGreaterEqualISy: IRes := ORD( Int1 >= Int2 );
GOTO LEndCase;
LNotEqualISy : IRes := ORD( Int1 <> Int2 );
GOTO LEndCase;
LEqualSSy: IRes := ORD( CompareStr( Str1 , Str2 ) = Equal );
GOTO LEndCase;
LLessEqualSSy: IRes := ORD( CompareStr( Str1 , Str2 ) <> Greater );
GOTO LEndCase;
LLessSSy: IRes := ORD( CompareStr( Str1 , Str2 ) = Less );
GOTO LEndCase;
LGreaterSSy: IRes := ORD( CompareStr( Str1 , Str2 ) = Greater );
GOTO LEndCase;
LGreaterEqualSSy: IRes := ORD( CompareStr( Str1 , Str2 ) <> Less );
GOTO LEndCase;
LNotEqualSSy : IRes := ORD( CompareStr( Str1 , Str2 ) <> Equal );
GOTO LEndCase;
LAndSy : IRes := Int1 AND Int2;
GOTO LEndCase;
LNotSy : IRes := NOT Int1;
GOTO LEndCase;
LOrSy : IRes := Int1 OR Int2;
GOTO LEndCase;
LXorSy : IRes := Int1 XOR Int2;
GOTO LEndCase;
LOrdSy : IRes := ORD( Str1[ Int1 ] );
GOTO LEndCase;
LChrSy : SRes := CHR( Int1 );
GOTO LEndCase;
LWaitFoundSy : IRes := ORD( Script_Wait_Found );
GOTO LEndCase;
LConnectedSy : IRes := ORD( Async_Carrier_Detect );
GOTO LEndCase;
LAttendedSy : IRes := ORD( Attended_Mode );
GOTO LEndCase;
LDialedSy : IRes := ORD( Script_Dialed );
GOTO LEndCase;
LFileExistsSy : BEGIN
(*$I-*)
ASSIGN( F , Str1 );
RESET ( F );
(*$I+*)
IRes := ORD( Int24Result = 0 );
(*$I-*)
CLOSE ( F );
(*$I+*)
Int1 := Int24Result;
END;
GOTO LEndCase;
LEofSy : BEGIN
IF Script_File_Used[Int1] THEN
IRes := ORD( Script_File_List[Int1]^.EOF_Seen )
ELSE
IRes := 1;
END;
GOTO LEndCase;
LStringSy : STR( Int1 , SRes );
GOTO LEndCase;
LNumberSy : BEGIN
VAL( TRIM( LTRIM( Str1 ) ), IRes, Int1 );
IF ( Int1 <> 0 ) THEN
IRes := 0;
END;
GOTO LEndCase;
LIOResultSy : IRes := Script_IO_Error;
GOTO LEndCase;
LDuplSy : SRes := Dupl( Str1[1], Int1 );
GOTO LEndCase;
LUpperCaseSy : SRes := UpperCase( Str1 );
GOTO LEndCase;
LTrimSy : SRes := Trim( Str1 );
GOTO LEndCase;
LLTrimSy : SRes := LTrim( Str1 );
GOTO LEndCase;
LParamCountSy : IRes := ParamCount;
GOTO LEndCase;
LParamStrSy : SRes := ParamStr( Int1 );
GOTO LEndCase;
LParamLineSy : MOVE( MEM[CSeg:$80], SRes, MEM[CSeg:$80] );
GOTO LEndCase;
LDateSy : SRes := DialDateString;
GOTO LEndCase;
LTimeSy : SRes := TimeString( TimeOfDay , Military_Time );
GOTO LEndCase;
LDialEntrySy : IF ( ( Int1 > 0 ) AND ( Int1 <= Dialing_Dir_Size ) ) THEN
BEGIN
SRes[0] := CHR( Dialing_Dir_Entry_Length );
MOVE( Dialing_Directory^[Int1], SRes[1],
Dialing_Dir_Entry_Length );
END
ELSE
SRes[0] := #0;
GOTO LEndCase;
LReadCtrlSy : SRes := Read_Ctrls ( Str1 );
GOTO LEndCase;
LWriteCtrlSy : SRes := Write_Ctrls( Str1 );
GOTO LEndCase;
{ END (* CASE *); }
LEndCase: ;
CASE ResTypeVector[Operator] OF
Integer_Variable_Type: Push_Stack_Integer( IRes );
String_Variable_Type : Push_Stack_String ( SRes );
ELSE;
END (* CASE *);
END (* Perform_Operator *);
(*----------------------------------------------------------------------*)
(* Get_Next_Operand --- Get next operand from postfix string *)
(*----------------------------------------------------------------------*)
PROCEDURE Get_Next_Operand( VAR Operand_Type : INTEGER;
VAR Index : INTEGER );
BEGIN (* Get_Next_Operand *)
Script_Buffer_Pos := SUCC( Script_Buffer_Pos );
Operand_Type := Script_Buffer^[Script_Buffer_Pos];
CASE Operands[Operand_Type] OF
Operator_Type,
Integer_Variable_Type,
String_Variable_Type: BEGIN
Script_Buffer_Pos := SUCC( Script_Buffer_Pos );
Index := Script_Buffer^[Script_Buffer_Pos];
END;
Integer_Constant_Type: BEGIN
Script_Buffer_Pos := SUCC( Script_Buffer_Pos );
MOVE( Script_Buffer^[Script_Buffer_Pos], Index, 2 );
Script_Buffer_Pos := SUCC( Script_Buffer_Pos );
END;
String_Constant_Type: Script_Buffer_Pos := SUCC( Script_Buffer_Pos );
END (* CASE *);
END (* Get_Next_Operand *);
(*----------------------------------------------------------------------*)
BEGIN (* Execute_Stack *)
{
IF Debug_Mode THEN
Debug_Write('+++ Entering Execute_Stack +++');
}
End_Of_Stack := FALSE;
Stack_Index := 0;
WHILE ( NOT End_Of_Stack ) DO
BEGIN
Get_Next_Operand( Operand_Type , Index );
CASE Operands[Operand_Type] OF
Integer_Variable_Type,
String_Variable_Type : Move_Variable_To_Stack( Index );
Integer_Constant_Type: Move_Integer_Constant_To_Stack( Index );
String_Constant_Type : Move_String_Constant_To_Stack ( Script_Buffer_Pos );
Operator_Type : Perform_Operator( OperSyms2[Index] );
StackEnd_Type : End_Of_Stack := TRUE;
END (* CASE *);
END;
WITH Script_Variables^[Result_Index] DO
BEGIN
CASE Var_Type OF
Integer_Variable_Type : BEGIN
Pop_Stack_Integer( Int1 );
Var_Value^ := CHR( Int1_Bytes[1] ) +
CHR( Int1_Bytes[2] );
END;
String_Variable_Type : BEGIN
Pop_Stack_String( Str1 );
Var_Value^ := Str1;
END;
ELSE
{
IF Debug_Mode THEN
Debug_Write('*** BOGUS RESULT MODE IN EXECUTE_STACK = ' +
ITOS( ORD( Var_Type ) ) );
}
;
END (* CASE *);
END;
{
IF Debug_Mode THEN
Debug_Write('+++ Leaving Execute_Stack +++');
}
END (* Execute_Stack *);
(*----------------------------------------------------------------------*)
PROCEDURE Do_Simple_If( Condit : BOOLEAN );
BEGIN (* Do_Simple_If *)
IF ( Script_Integer_1 = 1 ) THEN
IF Condit THEN
Script_Buffer_Pos := PRED( Script_Integer_2 )
ELSE
Script_Buffer_Pos := PRED( Script_Integer_3 )
ELSE
IF ( NOT Condit ) THEN
Script_Buffer_Pos := PRED( Script_Integer_2 )
ELSE
Script_Buffer_Pos := PRED( Script_Integer_3 );
END (* Do_Simple_If *);
(*--------------------------------------------------------------------------*)
(* Fix_Up_File_Name --- Get file name for edit/view operation *)
(*--------------------------------------------------------------------------*)
PROCEDURE Fix_Up_File_Name( File_Function: AnyStr;
Path : AnyStr;
VAR Jump_Text : AnyStr );
VAR
FName : FileStr;
IPos : INTEGER;
BEGIN (* Fix_Up_File_Name *)
(* Save screen *)
Save_Partial_Screen( Saved_Screen, 5, 10, 75, 14 );
Draw_Menu_Frame( 5, 10, 75, 14, Menu_Frame_Color, Menu_Title_Color,
Menu_Text_Color, File_Function + ' File');
(* Get name of file to edit *)
FName[0] := CHR( 0 );
WRITELN('Enter name of file to ', File_Function, ':');
WRITE('>');
Read_Edited_String( FName );
WRITELN;
(* Restore screen *)
Restore_Screen( Saved_Screen );
Reset_Global_Colors;
(* Replace file name marker in path *)
(* with file name just obtained *)
IF ( FName <> CHR( ESC ) ) THEN
BEGIN
Jump_Text := Path;
IPos := POS( '%F' , Jump_Text );
WHILE( IPos > 0 ) DO
BEGIN
DELETE( Jump_Text, IPos, 2 );
INSERT( FName, Jump_Text, IPos );
IPos := POS( '%F' , Jump_Text );
END;
END
ELSE
Jump_Text[0] := CHR( 0 );
END (* Fix_Up_File_Name *);
(*--------------------------------------------------------------------------*)
(* Allocate_Variable --- Allocate variable if necessary *)
(*--------------------------------------------------------------------------*)
PROCEDURE Allocate_Variable;
VAR
NBytes : INTEGER;
P : Script_Save_Variable_Record_Ptr;
BEGIN (* Allocate_Variable *)
{
IF Debug_Mode THEN
Debug_Write('--- Allocating variable # ' + ITOS( Script_Integer_1 ) +
' = ' + Script_String + ' of type = ' + ITOS( Script_Integer_2 ) );
}
(* Save previous var at this offset *)
(* if in CALLed procedure *)
IF ( Script_Call_Depth > 0 ) THEN
WITH Script_Call_Stack[Script_Call_Depth] DO
BEGIN
P := Save_Vars;
NEW( Save_Vars );
Save_Vars^.Prev_Var := P;
NEW( Save_Vars^.Save_Data );
Save_Vars^.Save_Data^ := Script_Variables^[Script_Integer_1];
{
IF Debug_Mode THEN
BEGIN
Debug_Write('--- Saving old variable ' + IToS( Script_Integer_1 ) );
Debug_Write(' Name = ' +
Script_Variables^[Script_Integer_1].Var_Name );
Debug_Write(' Call depth = ' +
IToS( Script_Call_Depth ) );
END;
}
END;
(* Allocate the variable *)
IF ( Command = DeclareSy ) THEN
WITH Script_Variables^[Script_Integer_1] DO
BEGIN
CASE Oper_Type_Vector[Script_Integer_2] OF
Integer_Variable_Type: NBytes := 3;
String_Variable_Type : NBytes := 256;
ELSE
{
IF Debug_Mode THEN
Debug_Write('===> WARNING, Bogus type in allocate = ' +
ITOS( Script_Integer_2 ) );
}
;
END (* CASE *);
GETMEM( Var_Value , NBytes );
Var_Value^ := Script_String_2;
Var_Name := Script_String;
Var_Type := Oper_Type_Vector[Script_Integer_2];
Var_Passed := FALSE;
END
ELSE IF ( Command = ImportSy ) THEN
BEGIN
Script_Parameter_Got := SUCC( Script_Parameter_Got );
Script_Variables^[Script_Integer_1] :=
Prev_Script_Variables^[Script_Parameters^[Script_Parameter_Got]];
Script_Variables^[Script_Integer_1].Var_Passed := TRUE;
END
ELSE (* PImportSy *)
BEGIN
Proc_Parameter_Got := SUCC( Proc_Parameter_Got );
Script_Variables^[Script_Integer_1] :=
Script_Variables^[Proc_Parameters^[Proc_Parameter_Got]];
Script_Variables^[Script_Integer_1].Var_Passed := TRUE;
END;
Script_Variable_Count := MAX( Script_Variable_Count , Script_Integer_1 );
END (* Allocate_Variable *);
(*--------------------------------------------------------------------------*)
(* Zap_Variables --- Zap script variables *)
(*--------------------------------------------------------------------------*)
PROCEDURE Zap_Script_Variables( First : INTEGER; Last : INTEGER );
VAR
I: INTEGER;
P: Script_Save_Variable_Record_Ptr;
V: INTEGER;
BEGIN (* Zap_Script_Variables *)
(* Free up variable memory *)
FOR I := Last DOWNTO First DO
WITH Script_Variables^[I] DO
IF ( NOT Var_Passed ) THEN
CASE Var_Type OF
Integer_Variable_Type: FREEMEM( Var_Value , 3 );
String_Variable_Type : FREEMEM( Var_Value , 256 );
ELSE;
END;
(* Restore old variable pointers *)
(* if necessary. *)
IF ( Script_Call_Depth > 0 ) THEN
WITH Script_Call_Stack[Script_Call_Depth] DO
FOR I := Last DOWNTO First DO
BEGIN
P := Save_Vars;
IF ( P <> NIL ) THEN
BEGIN
Script_Variables^[I] := P^.Save_Data^;
Save_Vars := P^.Prev_Var;
DISPOSE( P^.Save_Data );
DISPOSE( P );
{
IF Debug_Mode THEN
BEGIN
Debug_Write('Restoring variable ' + IToS( I ));
Debug_Write(' Name = ' + Script_Variables^[I].Var_Name );
CASE Script_Variables^[I].Var_Type OF
Integer_Variable_Type : BEGIN
Debug_Write(' Type = INTEGER' );
MOVE( Script_Variables^[I].Var_Value^[1], V, 2 );
Debug_Write(' Value = ' + IToS( V ) );
END;
String_Variable_Type : BEGIN
Debug_Write(' Type = STRING');
Debug_Write(' Value = ' +
Script_Variables^[I].Var_Value^ );
END;
END (* CASE *);
Debug_Write(' Call depth = ' +
IToS( Script_Call_Depth ) );
END;
}
END;
END;
(* Restore old variable count *)
Script_Variable_Count := PRED( First );
{
IF Debug_Mode THEN
Debug_Write( 'Zap: First = ' + IToS( First ) + ', Last = ' +
IToS( Last ) + ', Count = ' + IToS( Script_Variable_Count ) );
}
END (* Zap_Script_Variables *);
(*--------------------------------------------------------------------------*)
(* Clear_Script_Variables --- Deallocate script variables *)
(*--------------------------------------------------------------------------*)
PROCEDURE Clear_Script_Variables;
VAR
I: INTEGER;
L: INTEGER;
S: AnyStr;
BEGIN (* Clear_Script_Variables *)
(* Free space for variable values *)
Zap_Script_Variables( 3 , Script_Variable_Count );
(* Free space for variable pointers *)
FREEMEM( Script_Variables ,
( Script_Variable_Count + 3 ) * SizeOf( Script_Variables^[1] ) );
(* No script variables active *)
Script_Variable_Count := 2;
Script_Parameter_Count := 0;
Script_Parameter_Got := 0;
(* Close all script files *)
FOR I := 1 TO MaxScriptOpenFiles DO
IF Script_File_Used[I] THEN
BEGIN
IF Script_File_List[I]^.Opened THEN
BEGIN
(*$I-*)
CLOSE( Script_File_List[I]^.F );
(*$I+*)
L := INT24Result;
END;
DISPOSE( Script_File_List[I] );
Script_File_Used[I] := FALSE;
END;
(* Turn off other script activities *)
FOR I := 1 TO Script_Wait_Count DO
WITH Script_Wait_List[I] DO
BEGIN
DISPOSE( Wait_Text );
DISPOSE( Wait_Reply );
END;
Script_File_Name[0] := CHR( 0 );
Script_Buffer := NIL;
Script_Dialed := FALSE;
Really_Wait_String := FALSE;
WaitString_Mode := FALSE;
Script_File_Count := 0;
Script_Wait_Count := 0;
Script_IO_Error := 0;
(* Clear out command line area. *)
S := CHR( CR );
MOVE( S[0], Mem[CSeg:$80], 2 );
END (* Clear_Script_Variables *);
(*--------------------------------------------------------------------------*)
(* Read_Chars --- Read characters from script-defined file *)
(*--------------------------------------------------------------------------*)
PROCEDURE Read_Chars( VAR F : Text_File;
VAR S : AnyStr;
N : INTEGER;
VAR EOF_Seen : BOOLEAN;
Use_KBD : BOOLEAN );
VAR
I : INTEGER;
J : INTEGER;
Ch: CHAR;
BEGIN (* Read_Chars *)
{
IF Debug_Mode THEN
BEGIN
Write_Log( 'N=' + CHR( ORD('0') + N ), FALSE, FALSE );
Write_Log( 'UK=' + CHR( ORD('0') + ORD(Use_KBD) ), FALSE, FALSE );
END;
}
IF EOF_Seen THEN
S[0] := CHR( 0 )
ELSE
BEGIN
I := 0;
WHILE ( ( I < N ) AND ( NOT EOF_Seen ) ) DO
BEGIN
(*$I-*)
CASE Use_KBD OF
FALSE: BEGIN
READ( F , Ch );
Script_IO_Error := INT24Result;
EOF_Seen := EOF( F ) OR ( Ch = ^Z );
END;
TRUE: BEGIN
READ( Kbd , Ch );
WRITE( Ch );
Script_IO_Error := INT24Result;
END;
END (* CASE *);
(*$I+*)
IF ( NOT EOF_Seen ) THEN
BEGIN
I := SUCC( I );
S[I] := Ch;
END;
END;
S[0] := CHR( I );
END;
END (* Read_Chars *);
(*--------------------------------------------------------------------------*)
(* Unload_This_Script --- Unload just-executed script *)
(*--------------------------------------------------------------------------*)
PROCEDURE Unload_This_Script;
VAR
I: INTEGER;
J: INTEGER;
BEGIN (* Unload_This_Script *)
I := Current_Script_Num;
FREEMEM( Scripts[I].Script_Ptr , Scripts[I].Script_Len );
FOR J := ( I + 1 ) TO Script_Count DO
MOVE( Scripts[J], Scripts[J-1], SizeOf( Scripts[1] ) );
Script_Count := PRED( Script_Count );
END (* Unload_This_Script *);
(*--------------------------------------------------------------------------*)
(* Exit_All_Scripts --- Exit all scripts regardless of nesting *)
(*--------------------------------------------------------------------------*)
PROCEDURE Exit_All_Scripts;
VAR
I: INTEGER;
BEGIN (* Exit_All_Scripts *)
REPEAT
(* Free space for variable values *)
Zap_Script_Variables( 3 , Script_Variable_Count );
(* Free space for variable pointers *)
FREEMEM( Script_Variables ,
( Script_Variable_Count + 3 ) * SizeOf( Script_Variables^[1] ) );
(* Free space for any parameters *)
IF ( Script_Parameter_Count > 0 ) THEN
DISPOSE( Script_Parameters );
WITH Script_Stack_Position[Script_Stack_Depth] DO
BEGIN
Script_Buffer := Buffer_Ptr;
Script_Buffer_Pos := Buffer_Pos;
Current_Script_Num := Script_Num;
Script_Variables := Vars_Ptr;
Script_Variable_Count := Vars_Count;
Script_Parameters := Params_Ptr;
Script_Parameter_Count := Params_Count;
Script_Parameter_Got := Params_Got;
Prev_Script_Variables := Prev_Ptr;
END;
Script_Stack_Depth := PRED( Script_Stack_Depth );
UNTIL ( Script_Stack_Depth = 0 );
(* Clear top-level scripts stuff *)
Clear_Script_Variables;
(* Indicate script mode turned off *)
Toggle_Option( 'Script Mode', Script_File_Mode );
END (* Exit_All_Scripts *);